home *** CD-ROM | disk | FTP | other *** search
-
-
-
-
-
-
-
-
-
-
-
-
-
- *******************************************
- * *
- * A STUDENT APPROACH TO *
- * COBOL ON AN IBM MVS/XA OPERATING SYSTEM *
- * *
- *******************************************
-
-
-
-
-
-
-
-
-
-
-
-
-
-
-
-
-
-
-
-
-
-
-
-
-
-
-
-
-
-
-
-
- John S. Ward
- 4/10/90
- Updated 8/21/91
-
- EJECT
- In this handout we follow step-by-step instructions in creating
- a COBOL program. Job Control Language (JCL) is used to demonstrate
- file linkage as well as program execution. For the purpose of this
- handout, we assume you have successfully accessed the ISPF/PDF
- PRIMARY OPTION MENU shown below:
-
- GEORGIA STATE UNIVERSITY COMPUTER CENTER
- --------------------ISPF/PDF PRIMARY OPTION MENU-----------------------
- OPTION ===>
- USER ID -userid
- 0 ISPF PARAMS -Specify terminal and user parameters TIME -14:42
- 1 BROWSE -Display source data or output listing TERMINAL -3278
- 2 EDIT -Create or change source data PF KEYS -24
- 3 UTILITIES -Perform utility functions
- 4 FOREGROUND -Invoke language procedures in foreground
- 5 BATCH -Submit job for language processing
- 6 COMMAND -Enter TSO command or CLIST
- 7 DIALOG TEST -Perform dialog testing
- 8 LM UTILITIES-Perform library management utility functions
- C CHANGE -Display summary of changes for this release
- T TUTORIAL -Display information about ISPF/PDF
- X EXIT -Terminate ISPF using log and list defaults
-
- Enter END command or PF3 to terminate ISPF.
-
-
-
- SECTION ONE: Creating your COBOL program.
-
-
- 1.1) Enter 6 at the "OPTION ===>" prompt of the ISPF/PDF PRIMARY OPTION
- MENU, and hit return to go to TSO COMMAND PROCESSOR panel.
-
- 1.2) Type CREATE at the cursor, and hit return. Next, type your initial
- when you are asked to "ENTER LIBRARY/APPLICATION NAME ===>". Hit
- return, and type COBOL at the next prompt. Hit return one more
- time when you see three asterisks displayed (hit return anytime
- you see *** displayed).
-
- 1.3) Use the F4 key to go back to the primary menu. Then, enter 2 at
- the "OPTION ===>" prompt to go to the EDIT - ENTRY PANEL.
- Fill the sections of this panel as shown below:
-
- EJECT
- ------------------------- EDIT - ENTRY PANEL ---------------------------
- COMMAND ===>
-
- ISPF LIBRARY:
- PROJECT ===> your userid
- GROUP ===> your initials ===> ===> ===>
- TYPE ===> COBOL
- MEMBER ===> program name (Blank for member selection list)
-
- OTHER PARTITIONED OR SEQUENTIAL DATA SET:
- DATA SET NAME ===>
- VOLUME SERIAL ===> (If not catalogued)
-
- DATA SET PASSWORD ===> (If password protected)
-
- PROFILE NAME ===> (Blank defaults to data set type)
-
-
- Hit return and you will see an empty file as shown below:
-
-
- EDIT --- User-id.Initial.COBOL(member) ------------- COLUMNS 001 072
- COMMAND ===> SCROLL ===>PAGE
- ****** *********************** TOP OF DATA **************************
- ''''''
- ''''''
- ''''''
- ''''''
- ''''''
- ''''''
- .
- .
-
-
- Type UNNUM at the cursor and hit return. Press the TAB key twice,
- type the letter "I" (insert), and hit return. Tab back then type
- COLS and press return. Use the right arrow key to move the cursor
- to the right. The first line of the body of a COBOL program will
- start in column 8. The first line in the body of the COBOL program
- will be the IDENTIFICATION DIVISION.
-
-
- EDIT --- User-id.Initial.COBOL(member) ------------- COLUMNS 001 072
- COMMAND ===> SCROLL ===>PAGE
- ****** ********************** TOP OF DATA ***************************
- =COLS>----+----1----+----2----+----3----+----4----+----5----+----6----+
- ''''''
- ****** *********************BOTTOM OF DATA **************************
- EJECT
- Press return followed by the HOME key. This will take your cursor
- back to the COMMAND line. Type the command RES which stands for
- RESEQUENCE. This will cause the rulers to disappear.
- Upon entering successive lines of text, the cursor will be placed
- under the first non blank character of the previous line. Since
- many of the lines of COBOL start in either column 8 or 12, this
- is most convenient. You don't need to use the cursor keys or
- space key near as much when entering successive lines of text.
-
- After typing your program you should press the home key and type
- the word SAVE on the COMMAND line. You may type CANCEL on the COMMAND
- line to leave the EDIT screen without saving your program or changes
- that you made to an existing program.
-
- In writing the File Description (FD) sections of your COBOL
- program, there are certain conventions that must be followed
- when interfacing with the IBM operating system. The FD phrase
- 'BLOCK CONTAINS 0 CHARACTERS' allows record and block size to be
- controlled by the Dataset Definition (DD) statements in the
- JCL rather than the COBOL program.
- Use the example below to help you with your own program.
-
- EDIT --- user-is.init.COBOL(TEST1) - 01.01 --------- COLUMNS 001 072
- COMMAND ===> SCROLL ===>PAGE
- ****** ******************** TOP OF DATA **************************
- 000001 //STEP1 EXEC COBUCLG
- 000002 IDENTIFICATION DIVISION.
- 000003 PROGRAM-ID. JOE-PROGRAMMER.
- 000004 DATE-COMPILED. JANUARY 5, 1993. 000005 ENVIRONMENT DIVISION.
- 000006 CONFIGURATION SECTION.
- 000007 SOURCE-COMPUTER. IBM-370.
- 000008 OBJECT-COMPUTER. IBM-370.
- 000009 INPUT-OUTPUT SECTION.
- 000010 FILE-CONTROL.
- 000011 SELECT INFILE ASSIGN TO UT-S-OLD.
- 000012 SELECT OUTFILE ASSIGN TO UT-S-NEW.
- 000013 DATA DIVISION.
- 000014 FILE SECTION.
- 000015 FD INFILE
- 000016 LABEL RECORDS ARE STANDARD
- 000017 BLOCK CONTAINS 0 CHARACTERS
- 000018 RECORD CONTAINS 56 CHARACTERS
- 000019 DATA RECORD IS INFILE.
- 000020 01 INFILE-COMPONENT.
- 000021 02 NAME PIC X(20).
- 000022 02 ACCT-NO PIC X(5).
- 000023 02 SSN PIC X(11).
- 000024 02 FILLER PIC X(20).
- 000025 FD OUTFILE
- 000026 LABEL RECORDS ARE STANDARD
- 000027 BLOCK CONTAINS 0 CHARACTERS
- 000028 RECORD CONTAINS 36 CHARACTERS
- 000029 DATA RECORD IS OUTFILE.
- 000030 01 OUTFILE-COMPONENT.
- 000031 02 NAME PIC X(20).
- 000032 02 ACCT-NO PIC X(5).
- 000033 02 SSN PIC X(11).
- 000034 WORKING-STORAGE SECTION.
- 000035 77 INFILE-STATUS PIC X(2).
- 000036 88 END-OF-FILE VALUE "10".
- 000037 PROCEDURE DIVISION.
- 000038 0000-MAIN.
- 000039 PERFORM 0010-INITIALIZE.
- 000040 PERFORM 0020-PROCESS-ONE-ACCOUNT UNTIL
- 000041 END-OF-FILE.
- 000042 PERFORM 0030-CLOSE.
- 000043 STOP RUN.
- 000044 0010-INITIALIZE.
- 000045 OPEN INPUT INFILE.
- 000046 OPEN OUTPUT OUTFILE.
- 000047 READ INFILE RECORD
- 000048 AT END MOVE "10" TO INFILE-STATUS.
- 000049 0020-PROCESS-ONE-ACCOUNT.
- 000050 MOVE CORR INFILE-COMPONENT TO
- 000051 OUTFILE-COMPONENT.
- 000052 WRITE OUTFILE-COMPONENT.
- 000053 READ INFILE RECORD
- 000054 AT END MOVE "10" TO INFILE-STATUS.
- 000055 0030-CLOSE.
- 000056 CLOSE INFILE.
- 000057 CLOSE OUTFILE.
- 000058 //GO.OLD DD DSN=userid.init.INDATA,DISP=SHR,
- 000059 // DCB=(BLKSIZE=56,RECFM=FB)
- 000060 //GO.NEW DD DSN=userid.init.OUTDATA,DISP=OLD,
- 000061 // DCB=(BLKSIZE=36,RECFM=FB)
- ****** ********************** BOTTOM OF DATA **************************
- EJECT
- In the example above, the lines that contain "//" in
- columns one and two, are the JCL statements. JCL statements
- perform the operations necessary to compile, link and execute
- your program.
- Notice that STEP1 executes a JCL procedure called COBUCLG.
- This procedure will compile, link, and execute a COBOL program.
- Within this procedure there are two steps called LNK and GO.
- JCL Dataset Definitions and library references may be inserted
- into the procedure by prefixing them with the step name followed
- by a period. The LNK step contains all the JCL necessary to
- to form an executable load module. The GO step contains all the
- JCL necessary in linking input and output data files.
- In the example above, GO.OLD tells the operating system that the
- internal link name OLD to which the logical file INFILE was
- assigned using the SELECT statement under the FILE-CONTROL section
- of the program is to be referenced to the Data Set Name (DSN) or
- the actual input file that you already created on disk.
- GO.NEW references the internal link name NEW to which OUTFILE
- was assigned by the SELECT statement under the FILE-CONTROL section.
- The Disposition of the file informs the operating system whether or
- not the file currently exists. The input file has a file disposition
- equal to SHR (DISP=SHR). The output file has a file disposition equal
- to OLD (DISP=OLD). This means that we have to create the input and
- output files before we execute our program.
-
- SECTION TWO: Creating your data files.
-
- 2.1) Type =3.2 at the "COMMAND ===>" prompt to go to the next panel.
- Use the TAB key to tab to the "TYPE ===>" prompt. Enter the name
- of your input file. Press the HOME key and enter "A" (for
- allocation) and press return. another panel will be displayed
- as the one shown below. Use these same parameters as input
- to your panel.
-
- ------------------------ ALLOCATE NEW DATA SET -------------------------
- COMMAND ===>
-
- DATA SET NAME: User-id.Initial.Type
-
- VOLUME SERIAL ===> (Blank for authorized default volume)
- SPACE UNITS ===>TRKS (BLKS, TRKS or CYLS)
- PRIMARY QUAN ===>1 (in above units)
- SECONDARY QUAN ===>1 (in above units)
- DIRECTORY BLOCKS===>0 (zero for sequential data set)
- RECORD FORMAT ===>FB
- RECORD LENGTH ===>56 << Sum of the pictures for this file >>
- BLOCK SIZE ===>56 << Sum of the pictures for this file >>
-
- For the RECORD LENGTH and BLOCK SIZE sections, enter the same
- number you used in the RECORD CONTAINS clause of this file.
- Then hit return to go back to the DATA SET UTILITY panel. Tab
- to the "TYPE ===>" prompt and enter the name of your output file.
- 2.2) Create your output file the same way you created your input file.
- EJECT
-
- SECTION THREE: Filling in your data.
-
- 3.1) Type =2 at the "OPTION ===>" prompt to go to EDIT panel. Enter
- the name of your input file. The file name should be entered
- at the "TYPE ===>" prompt. This name has to be the same
- as the one used in the DSN parameter of your input file. Now,
- press return to enter your input data.
-
- 3.2) Press the return key. Your screen should now have two rows of
- asterisks. Move you cursor to the first asterisk on the first
- line and type the letter I. After pressing return you will
- subsequently be prompted for each line of data. If no data
- is entered prompting will stop. You may then move your cursor
- to a line number while typing the letter I in order to resume
- prompting.
-
- 3.3) When you are finished creating your input file, go back to the
- EDIT - ENTRY PANEL by typing =2. At the "COMMAND ===>" prompt,
- type the name of your output file (this name should be the same
- one used in the DSN parameter).
- Next, hit return, and type SAVE to save the empty output file.
-
- SECTION FOUR: Executing your COBOL program.
-
-
- 4.1) To execute your program, enter =2 at the "COMMAND ===>" prompt.
- Hit return to go to the EDIT - ENTRY PANEL.
-
- 4.2) Enter the word COBOL at the "TYPE ===>" prompt of this panel.
- Then, enter the name of your COBOL program at the "MEMBER ===>"
- prompt. Press return and your program will be displayed at
- the terminal.
-
- 4.3) Enter the command 'SUBT A,10' at the "COMMAND ===>" prompt of
- this panel and press return to submit your program to the system.
- The "A" is the jobname character that will be suffixed to
- your userid. The batch job is to use no more than 10 seconds
- of central processing time.
-
- EJECT
- EDIT --- user-is.init.COBOL(TEST1) - 01.01 --------- COLUMNS 001 072
- COMMAND ===> SUBT A,10 SCROLL ===>PAGE
- ****** ******************** TOP OF DATA **************************
- 000001 //STEP1 EXEC COBUCLG
- 000002 IDENTIFICATION DIVISION.
- 000003 PROGRAM-ID. JOE-PROGRAMMER.
- 000004 DATE-COMPILED. MAY 5, 1990.
- 000005 ENVIRONMENT DIVISION.
- 000006 CONFIGURATION SECTION.
- 000007 SOURCE-COMPUTER. IBM-370.
- 000008 OBJECT-COMPUTER. IBM-370.
- 000009 INPUT-OUTPUT SECTION.
- 000010 FILE-CONTROL.
- .
- .
- .
- .
- 000053 READ INFILE RECORD
- 000054 AT END MOVE "10" TO INFILE-STATUS.
- 000055 0030-CLOSE.
- 000056 CLOSE INFILE.
- 000057 CLOSE OUTFILE.
- 000058 //GO.OLD DD DSN=userid.init.INDATA,DISP=SHR,
- 000059 // DCB=(BLKSIZE=56,RECFM=FB)
- 000060 //GO.NEW DD DSN=userid.init.OUTDATA,DISP=OLD,
- 000061 // DCB=(BLKSIZE=36,RECFM=FB)
- ****** ********************** BOTTOM OF DATA **************************
-
- Then, hit return, and you will see
-
- IKJ56250I JOB useridA(JOBnumber) SUBMITTED
- ***
-
- EJECT
- SECTION FIVE: Accessing your job output.
-
- 5.1) At the "COMMAND ===>" prompt, type =o.h to go to the SDSF or System
- Display and Search Facility PANEL H option.
-
- _____________________________________________________________________________
- |SDSF HELD OUTPUT DISPLAY ALL CLASSES 406 LINES LINE 1-1 (1)
- |COMMAND INPUT ===> SCROLL ===> HALF
- |NP JOBNAME TYPE JNUM #DSNS CRDATE C FCB DEST ROUTE #RECORDS RNUM RD-
- | S USERIDA JOB 1139 5 8/15/91 X **** GSUMVS1 350 0275
- |____________________________________________________________________________
-
-
-
-
-
- 5.2) Tab to the field under the NP heading and type in the letter
- S to view you job output.
-
-
- Below is a facsimile of a successful COBOL execution as viewed
- from the SDSF menu option H.
-
- BROWSE - USGHND.DAY.SPF235.OUTLIST ------------ LINE 000000 COL 001 080
- COMMAND ===> SCROLL ===>HALF
- ********************************** TOP OF DATA ************************
- 1 J E S 2 J O B L O G -- S Y S T E M G S U 1 -- N O
- 0
- 11.12.36 JOB 2185 ICH70001I USGHND LAST ACCESS AT 11:09:25 ON TUESDAY, OC
- 11.12.36 JOB 2185 $HASP373 USGHNDX STARTED - INIT A - CLASS A - SYS GSU1
- 11.12.45 JOB 2185 - --TIMING
- (
- 11.12.45 JOB 2185 -JOBNAME STEPNAME PROCSTEP RC EXCP CONN CPU
- 11.12.45 JOB 2185 -USGHNDX COB 00 332 1851 .00
- 11.12.45 JOB 2185 -USGHNDX LKED 00 332 1851 .00
- 11.12.45 JOB 2185 -USGHNDX GO 00 332 1851 .00
- 11.12.45 JOB 2185 -USGHNDX ENDED. NAME-USGHND /\ TOTAL CPU TIME=
- 11.12.46 JOB 2185 $HASP395 USGHNDX ENDED ]]
- 0------ JES2 JOB STATISTICS ------ ]]
- - 18 OCT 88 JOB EXECUTION DATE ]]-------------------
- - 9 CARDS READ ] A RETURN CODE (RC)
- - 152 SYSOUT PRINT RECORDS ] OF ZERO MEANS YOUR
- - 0 SYSOUT PUNCH RECORDS ] PROGRAM EXECUTED
- - 8 SYSOUT SPOOL KBYTES ] WITHOUT ERRORS.
- - 0.17 MINUTES EXECUTION TIME ]
- 1 //USGHNDX JOB I994998,USGHND, ]--------------------
- // NOTIFY=USGHND,CLASS=A,MSGLEVEL=(1,1),
- // USER=USGHND,TIME=(0,5)
-
-
-
- 5.3) To print your output file, type O under the NP heading. Your output
- will normally be printed on one of the production laser printers
- located on the ground floor of the Library South building. You can
- change the destination by toggling to the field under the DEST header
- and overlaying the GSUMVS1 destination. For example, if you want
- your output printed on the high-speed printer located in LS109,
- overlay the GSUMVS1 with TRM1.
- See the SDSF handout for further information.
-
- SECTION SIX: Logging off.
-
- To logoff, enter =X at the "COMMAND ===>" or "OPTION ===>"
- prompt of any panel. Once the operating system displays the
- message READY, you may then type the command LOGOFF.
- At this point you will be disconnected from the system.
-
- IMPORTANT NOTE:
-
- The program, input and output files that you have created are
- saved in the system. Therefore subsequent executions should
- reference sections 4.1 through 5.4.
- EJECT
- METHODS OF DEBUGGING
-
- There are two popular ways to debug a COBOL program on the
- MVS operating system.
-
- METHOD #1:
-
- If the program compiles with no syntax errors, but continues
- to execute beyond the time allocated on the SUBT command, the
- program may be in an infinite loop. In order to isolate the
- looping pattern you may make use of the COBOL statement
- READY TRACE. This command is always placed in column 12
- of your program and is placed, just like any other COBOL
- statement, within a paragraph. Upon execution of the program,
- the name of each paragraph will be written to your SYSOUT.
- With this information, you may be able to establish some sort
- of looping pattern based on the names of the paragraphs.
- The READY TRACE statement requires an additional line of JCL
- in order to work. This statement should be typed at the bottom
- of your program as follows:
-
- //SYSOUT DD SYSOUT=*
-
- METHOD #2:
-
- If you want to take a peek at a given variable in your program,
- you may do this using the COBOL DISPLAY statement. If you have
- a variable named CNTR, you may look at the contents of this
- variable using the DISPLAY statement. It might look as follows:
-
- DISPLAY CNTR.
-
- The DISPLAY statement also starts in column 12. The DISPLAY
- statement also requires an additional line of JCL in order to
- work. This statement should be typed at the bottom of your
- program as follows:
-
- //SYSOUT DD SYSOUT=*
-
- EJECT
- COMMONLY GENERATED ERROR MESSAGES
-
-
- 1) If you are getting a QSAM error message from the JCL, Job Control
- Language, then check to make sure the following are correct:
-
- A) Make sure the record size within your program matches the
- record size of the file on disk.
-
- B) Make sure the block size within your program matches the
- block size of the file on disk.
-
- C) Make sure that for every FD, File Description, there exist
- a 'BLOCK CONTAINS 0 CHARACTERS'.
-
- EJECT
-
- COMMONLY USED FEATURES OF THE FILE EDITOR
- ISPF/PDF
-
- PROGRAM
- FUNCTION KEYS NOTE: The more frequently used keys have
- been marked with an asterisk
- F1 HELP
- F2 SPLIT SCREEN
- * F3 END
- F4 RETURN
- F5 RFIND
- F6 RCHANGE
- * F7 UP SCREEN
- * F8 DOWN SCREEN
- F9 SWAP
- * F10 LEFT SCREEN
- * F11 RIGHT SCREEN
- F12 CURSOR
-
- ------------------------------------------------------------------------
-
-
- ISPF/PDF
- MENUS
-
- * =2 EDIT
- =3.1 DELETE MEMBERS
- =3.2 DELETE DATA SETS
- =3.4 GET LISTING OF ALL DATA SETS
- =3.6 GET PROGRAMS OF DATA FILES SENT TO PRINTER
-
- * =X EXIT OR LOGOFF SYSTEM (then type: logoff)
-
-
- ------------------------------------------------------------------------
-
- KEYBOARD NOTES
-
- ***** WHENEVER PROMPTED WITH '***' PRESS RETURN *****
- ***** IF PROMPTED WITH "READY" TO GET BACK ON THE *****
- ***** SYSTEM TYPE "ICF", OR IF YOU ARE FINISHED *****
- ***** TYPE "LOGOFF". *****
-
- ***** IF KEYBOARD FREEZES, PRESS THE TAB KEY *****
- ***** IF STILL FROZEN, PRESS THE return key *****
- ***** IF STILL FROZEN, PRESS CNTL G *****
- ***** IF KEYBOARD IS STILL LOCKED UP, PRESS ALT 2 *****
- ***** IF KEYBOARD IS STILL LOCKED UP, PRESS ALT 1 *****
-
- ------------------------------------------------------------------------
-
-